InitSpatialAveragePlants Subroutine

public subroutine InitSpatialAveragePlants(fileini, pathout, lai, gpp, npp, stem, root, leaf, cover, dbh, height, density, stemyield)

Initialization of spatial average of plants dynamic variables

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileini
character(len=*), intent(in) :: pathout
type(grid_real), intent(in) :: lai

leaf area index (m2/m2)

type(grid_real), intent(in) :: gpp

gross primary production (t)

type(grid_real), intent(in) :: npp

net primary production (t)

type(grid_real), intent(in) :: stem

stem biomass (t)

type(grid_real), intent(in) :: root

root biomass (t)

type(grid_real), intent(in) :: leaf

foliage biomass (t)

type(grid_real), intent(in) :: cover

canopy cover (0-1)

type(grid_real), intent(in) :: dbh

diameter at brest heigth (cm)

type(grid_real), intent(in) :: height

tree height (m)

type(grid_real), intent(in) :: density

tree density (tree/hectare)

type(grid_real), intent(in) :: stemyield

stem yield (t)


Variables

Type Visibility Attributes Name Initial
type(IniList), public :: iniDB

Source Code

SUBROUTINE InitSpatialAveragePlants   & 
!
 (fileini, pathout, lai, gpp, npp, stem, root, leaf, cover, dbh, height, &
    density, stemyield)  

IMPLICIT NONE

!arguments with intent in:
CHARACTER(LEN = *), INTENT(IN) :: fileini 
CHARACTER(LEN = *), INTENT(IN) :: pathout     
TYPE (grid_real), INTENT(IN)   :: lai !!leaf area index (m2/m2)
TYPE (grid_real), INTENT(IN)   :: gpp !!gross primary production (t)
TYPE (grid_real), INTENT(IN)   :: npp !!net primary production (t)
TYPE (grid_real), INTENT(IN)   :: stem !!stem biomass (t)
TYPE (grid_real), INTENT(IN)   :: root !!root biomass (t)
TYPE (grid_real), INTENT(IN)   :: leaf !!foliage biomass (t)
TYPE (grid_real), INTENT(IN)   :: cover !!canopy cover (0-1)
TYPE (grid_real), INTENT(IN)   :: dbh !!diameter at brest heigth (cm)
TYPE (grid_real), INTENT(IN)   :: height !!tree height (m)
TYPE (grid_real), INTENT(IN)   :: density !!tree density (tree/hectare)
TYPE (grid_real), INTENT(IN)   :: stemyield !!stem yield (t)

!local declarations
TYPE(IniList)          :: iniDB
!-------------------------------end of declaration-----------------------------

!  open and read configuration file
CALL IniOpen (fileini, iniDB) 

! search for active variable for output
CALL Catch ('info', 'SpatialAverage', 'checking for plants active variables ')

countplants = 0

!leaf area index
IF ( IniReadInt ('lai', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (lai % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'lai not allocated, &
                                            forced to not export spatial average ')
       plantsout (1) = .FALSE.
   ELSE
       plantsout (1) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (1) = .FALSE.
END IF


!gross primary production
IF ( IniReadInt ('gpp', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (gpp % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'gpp not allocated, &
                                            forced to not export spatial average ')
       plantsout (2) = .FALSE.
   ELSE
       plantsout (2) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (2) = .FALSE.
END IF


!net primary priduction
IF ( IniReadInt ('npp', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (npp % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'npp not allocated, &
                                            forced to not export spatial average ')
       plantsout (3) = .FALSE.
   ELSE
       plantsout (3) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (3) = .FALSE.
END IF


!stem biomass
IF ( IniReadInt ('stem', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (stem % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'stem biomass not allocated, &
                                            forced to not export spatial average ')
       plantsout (4) = .FALSE.
   ELSE
       plantsout (4) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (4) = .FALSE.
END IF


!root biomass
IF ( IniReadInt ('root', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (root % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'root biomass not allocated, &
                                            forced to not export spatial average ')
       plantsout (5) = .FALSE.
   ELSE
       plantsout (5) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (5) = .FALSE.
END IF


!leaf biomass
IF ( IniReadInt ('leaf', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (leaf % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'leaf biomass not allocated, &
                                            forced to not export spatial average ')
       plantsout (6) = .FALSE.
   ELSE
       plantsout (6) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (6) = .FALSE.
END IF


!canopy cover
IF ( IniReadInt ('cover', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (cover % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'canopy cover not allocated, &
                                            forced to not export spatial average ')
       plantsout (7) = .FALSE.
   ELSE
       plantsout (7) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (7) = .FALSE.
END IF


!diameter at brest heigth
IF ( IniReadInt ('dbh', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (dbh % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'dbh not allocated, &
                                            forced to not export spatial average ')
       plantsout (8) = .FALSE.
   ELSE
       plantsout (8) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (8) = .FALSE.
END IF


!tree height
IF ( IniReadInt ('height', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (height % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'height not allocated, &
                                            forced to not export spatial average ')
       plantsout (9) = .FALSE.
   ELSE
       plantsout (9) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (9) = .FALSE.
END IF


!tree density
IF ( IniReadInt ('density', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (density % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'density not allocated, &
                                            forced to not export spatial average ')
       plantsout (10) = .FALSE.
   ELSE
       plantsout (10) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (10) = .FALSE.
END IF


!stem yield
IF ( IniReadInt ('stem-yield', iniDB, section = 'plants') == 1) THEN
   IF ( .NOT. ALLOCATED (stemyield % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'stem yield not allocated, &
                                            forced to not export spatial average ')
       plantsout (11) = .FALSE.
   ELSE
       plantsout (11) = .TRUE.
       countplants = countplants + 1
   END IF
ELSE
   plantsout (11) = .FALSE.
END IF



plantsInitialized = .TRUE.

CALL IniClose (iniDB) 

CALL ConfigureExtents (fileini, pathout)


RETURN
END SUBROUTINE InitSpatialAveragePlants